home *** CD-ROM | disk | FTP | other *** search
- ;===================================================
- ; module ZapStuff
- ;
- ; Module of external procedures for Turbo Pascal.
- ; Provides high speed direct write screen output.
- ;
- ; In Turbo, declare as:
- ;
- ; procedure ZapStuff;
- ; external 'zapstuff.com';
- ;
- ; procedure ZapStr(var Str: AnyString; Row, Column, Attribute, Video: byte);
- ; external zapstuff[0];
- ;
- ; procedure ZapClrEOL(Row, Column, Attribute, Video: byte);
- ; external zapstuff[3];
- ;
- ; procedure ZapClrBox(ulrow, ulcolumn, lrrow, lrcol, attribute: byte);
- ; external zapstuff[6];
- ;
- ; See page 211 of the Turbo Pascal version 3 manual for
- ; a discussion of this declaration syntax.
- ;===================================================
-
- bios_data equ 40H
- equip_flag equ [10H]
- crt_status equ 3DAH ;crt status port on 6845 controller chip
- mono_seg equ 0B000H
- color_seg equ 0B800H
-
- ;==========================================================
- ; The following structures mimic the contents of the stack
- ; for calls to each of the procedures. Note that byte
- ; parameters occupy an entire word on the stack.
- ;==========================================================
-
- strstack struc ;simulate stack contents
- str_old_bp dw 0000H ;saved bp register
- str_ret_addr dw 0000H ;return address to turbo pascal
- str_video dw 0000H ;5th param: video output method
- str_attrib dw 0000H ;4th param: attribute byte
- str_col dw 0000H ;3rd param: column
- str_row dw 0000H ;2nd param: row
- str_str_offs dw 0000H ;1st param: offset of string
- str_str_seg dw 0000H ;1st param: segment of string
- endstruc
-
- eolstack struc
- eol_old_bp dw 0000H ;saved bp register
- eol_ret_addr dw 0000H ;return address to turbo pascal
- eol_video dw 0000H ;4th param: video output method
- eol_attrib dw 0000H ;3rd param: video attribute
- eol_col dw 0000H ;2nd param: column
- eol_row dw 0000H ;1st param: row
- endstruc
-
- cbstack struc
- cb_old_bp dw 0000H ;saved bp register
- cb_ret_addr dw 0000H ;return address to turbo pascal
- cb_attrib dw 0000H ;5th param: video attribute
- cb_lrc dw 0000H ;4th param: lower right column
- cb_lrr dw 0000H ;3rd param: lower right row
- cb_ulc dw 0000H ;2nd param: upper left column
- cb_ulr dw 0000H ;1st param: upper left row
- endstruc
-
- ;==================================
- ; Entry Point
- ;
- ; Jump table to various procedures
- ;==================================
- org 0
- enterstr jmp zapstr ;print a string
- enterclreol jmp zapclreol ;clear to the end of line
- enterclrbox jmp zapclrbox ;clear out a defined area
-
- ;=======================================================================
- ; procedure ZapStr(var Str: AnyString; Row, Column, Attribute, Video: byte);
- ;
- ; Outputs a string at the specified screen location, using the given attribute.
- ;
- ; The output method depends on the value of parameter VIDEO:
- ;
- ; 0 = direct write to hardware, no delay
- ; 1 = direct write to hardware, but only during screen retrace
- ; 2 = write via BIOS
- ;========================================================================
- zapstr proc near
-
- push bp ;establish stack
- mov bp, sp ; addressability
- push ds ;save state
- push es ; ditto
-
- lds si, str_str_offs[bp] ;set up to access string
- xor ch, ch ;CX <== length of string
- mov cl, [si] ; ditto
- cmp cl, 0 ;any characters to write?
- je str_exit ;exit if not
- inc si ;SI <== pointer to first char
-
- mov dl, str_video[bp] ;which video method?
- cmp dl, 2 ; -BIOS calls?
- jl str_direct ; if not use direct write
- call str_bios ; if so, use bios calls
- jmps str_exit ; and exit
- ;=====================================
- ; Set up for both direct write flavors
- ; After this fragment, the following
- ; register assignments hold:
- ;
- ; ES:DI pointer into video buffer
- ; DS:SI pointer to 1st string character
- ; CX: length of string
- ; AH: video attribute byte
- ; DL: video output method
- ;=====================================
- str_direct xor ah, ah ;AX <== column number
- mov al, str_col[bp] ;get column
- xor bh, bh ;BX <== row number
- mov bl, str_row[bp] ;get row
- call calc_offset ;DI <== offset into buffer
- call set_video_seg ;set up ES to access video buffer
- mov ah, str_attrib[bp] ;AH <== video attribute
- jc str_use_dw ;monochrome always direct write
- rcr dl ;retrace only mode?
- jc str_use_dwr ;yes
- str_use_dw call str_dw ;else use direct write
- jmps str_exit ;and done
- str_use_dwr call str_dwr ;use direct write/retrace
- ;fall through to exit
-
- str_exit pop es ;restore state
- pop ds ; ditto
- pop bp ; ditto
- ret 12 ;clear params and return
- endp ;zapstr
- ;=================================================
- ; STR_BIOS
- ;
- ; Write string to the screen using BIOS calls.
- ; Slow as a dog, but safe.
- ;
- ; Assumptions:
- ;
- ; DS:SI pointer to string
- ; CX length of string
- ;==================================================
- str_bios proc near
- mov di, cx ;DI <== string length
-
- mov ah, 03 ;get current cursor position
- mov bh, 0 ;active page number
- int 10H ;call BIOS
- push dx ;save cursor position for restore
-
- mov dl, str_col[bp] ;get column
- dec dl ;correct for 0,0 origin
- mov dh, str_row[bp] ;get row
- dec dh ;correct for 0,0 origin
- mov bl, str_attrib[bp] ;get attribute byte
-
- mov cx, 1 ;write only one char per call
- mov bh, 0 ;work on page 0
- str_bios_loop mov ah, 2 ;set cursor position
- int 10H ;with BIOS call
-
- lodsb ;AH <== next character
- mov ah, 9 ;write char/attrib
- int 10H ;with BIOS call
-
- inc dl ;bump current column
- dec di ;used up one char
- jnz str_bios_loop ;loop til out of chars
-
- pop dx ;restore cursor
- mov ah, 2 ; ditto
- int 10H ; ditto
- ret ;and return
- endp
-
- ;====================================================
- ; Str_DW
- ;
- ; Full speed direct write of string to video buffer.
- ;
- ; Assumptions:
- ;
- ; DS:SI points to first character of string
- ; ES:DI points to desired location in video buffer
- ; CX has length of string
- ; AH has desired video attribute byte
- ;
- ; Note that we read char *bytes* from the string,
- ; but write char/attrib *words* to buffer.
- ;====================================================
- str_dw proc near
- cld ;8088 --> autoincrement mode
- str_dw_loop lodsb ;get a char from string
- stosw ;put char and attrib in buffer
- loop str_dw_loop ;continue till done
- ret ;done, so exit
- endp
- ;====================================================
- ; Str_DWR
- ;
- ; String direct write during retrace.
- ;
- ; Assumptions:
- ;
- ; DS:SI points to first character of string
- ; ES:DI points to desired location in video buffer
- ; CX has length of string
- ; AH has desired video attribute byte
- ;=====================================================
- str_dwr proc near
- ;preload stuff for fast action
- mov bh, 9 ;mask to detect both retraces
- mov dx, crt_status ;pointer to crt controller chip
-
- cld ;8088 --> autoincrement mode
- str_stall in al, dx ;throw away any current horiz.
- rcr al ;retrace so we catch the next
- jc str_stall ;*full* one. This one may be
- ;half over already.
-
- lodsb ;get the next char
- mov bl, al ;save it, we need AL
- cli ;we're busy, let the phone ring
- str_wait in al, dx ;watch for retrace
- and al, bh ;either horiz or vert
- jz str_wait ;not yet? loop
-
- mov al, bl ;recover char
- stosw ;stuff it into the buffer
- sti ;answer the phone
- loop str_stall ;loop til done
- ret
- endp
-
- ;============================================
- ; ZapClrEOL
- ;
- ; Starting from the indicated row and column,
- ; clear to the end of the line.
- ;============================================
- zapclreol proc near
- push bp ;establish stack
- mov bp, sp ; addressability
- push ds ;save state
- push es ; ditto
-
- mov dl, eol_video[bp] ;which video method?
- cmp dl, 2 ;bios call?
- jne eol_direct ;if not, use direct write
- call eol_bios ;otherwise use bios calls
- jmps eol_exit
-
- ;======================================
- ; Set up for both direct write flavors
- ;======================================
- eol_direct mov cx, 81 ;calculate bytes to clear
- mov ax, eol_col[bp] ;AX <== column
- mov bx, eol_row[bp] ;BX <== row
- sub cx, ax ;CX <== bytes to clear
-
- call calc_offset ;DI <== offset into buffer
- call set_video_seg ;set up ES to access video buffer
- mov ah, eol_attrib[bp] ;AH <== video attribute
- mov al, ' ' ;fill with spaces
- jc eol_use_dw ;monochrome always direct write
- rcr dl ;retrace only mode?
- jc eol_use_dwr ;yes
- eol_use_dw call eol_dw ;no, use direct write
- jmps eol_exit ;then exit
- eol_use_dwr call eol_dwr ;use write during retrace
- jmps eol_exit ;then exit
-
- eol_exit pop es ;restore state
- pop ds ; ditto
- pop bp ; ditto
- ret 8 ;clear params and return
- endp ;zapclreol
-
- ;===============================================
- ; Char_DW
- ;
- ; Direct write of character(s) to video buffer.
- ; Assumptions:
- ;
- ; ES:DI pointer into video buffer
- ; AX char/attribute
- ; CX repetition factor
- ;===============================================
- eol_dw proc near
- cld ;8088 <== autoincrement mode
- rep ;do it
- stosw
- ret
- endp
-
- ;===============================================
- ; EOL_DWR
- ;
- ; Direct write of character(s) to video buffer,
- ; during retrace interval.
- ; Assumptions:
- ;
- ; ES:DI pointer into video buffer
- ; AX char/attribute
- ; CX repetition factor
- ;===============================================
- eol_dwr proc near
- ;preload stuff for fast action
- mov bl, al ;save character
- mov bh, 9 ;mask to detect both retraces
- mov dx, crt_status ;pointer to crt controller chip
- cld ;8088 --> autoincrement mode
-
- eol_stall in al, dx ;throw away any current horiz.
- rcr al ;retrace so we catch the next
- jc eol_stall ;*full* one. This one may be
- ;half over already.
-
- cli ;we're busy, let the phone ring
- eol_wait in al, dx ;watch for retrace
- and al, bh ;either horiz or vert
- jz eol_wait ;not yet? loop
-
- mov al, bl ;recover char
- stosw ;stuff it into the buffer
- sti ;answer the phone
- loop eol_stall ;loop til done
- ret
- endp
-
- ;=============================================
- ; EOL_BIOS
- ;
- ; Write character(s) to screen using BIOS call.
- ;=============================================
- eol_bios proc near
- mov ah, 03 ;current cursor position?
- mov bh, 0 ; on page 0
- int 10H ; with BIOS call
- push dx ; save position on stack
-
- mov cx, 81 ;calculate bytes to clear
- mov dx, eol_col[bp] ;AX <== column
- mov ax, eol_row[bp] ;DX <== row
- sub cx, dx ;CX <== bytes to clear
-
- mov dh, al ;DH,DL <== row, column
- dec dh ;correct for 0,0 origin
- dec dl ; ditto
-
- mov ah, 2 ;set cursor position
- mov bh, 0 ;work on page 0
- int 10H
-
- mov al, ' ' ;fill with space chars
- mov bl, eol_attrib[bp] ;get video attribute for clear
- mov ah, 9 ;call BIOS for write operation
- int 10H
-
- mov ah, 02 ;restore cursor position
- mov bh, 0 ; ditto
- pop dx ; ditto
- int 10H ; ditto
-
- ret ;and exit
- endp
-
- ;==============================================
- ; ZapClrBox
- ;
- ; Clears the specifed area of the video screen.
- ;==============================================
- zapclrbox proc near
- push bp ;establish stack
- mov bp, sp ; addressability
-
- mov ch, cb_ulr[bp] ;define upper left corner
- dec ch ;BIOS defines upper left 0,0
- mov cl, cb_ulc[bp] ;
- dec cl
- mov dh, cb_lrr[bp] ;define lower right corner
- dec dh
- mov dl, cb_lrc[bp] ; ditto
- dec dl
- mov bh, cb_attrib[bp] ;attribute to fill with
- mov ax, 0600H ;scroll entire window up
-
- int 10H ;call bios
-
- pop bp ; ditto
- ret 10 ;clear params and return
- endp ;zapclreol
- ;===========================================
- ; SET_VIDEO_SEG
- ;
- ; Points ES at the appropriate video buffer
- ; depending on which display adapter is installed.
- ; Returns with carry flag clear if color card,
- ; set for monochrome.
- ;===========================================
- set_video_seg proc near ;points ES at video buffer
- push ds ;set up to read equipment flag
- mov ax, bios_data ; ditto
- mov ds, ax ; ditto
- mov ax, equip_flag ;get flag
- and ax, 30H ;look at monitor bits only
- cmp ax, 30H ;is this the monochrome monitor?
- je set_video_mono ;yep, skip.
- mov ax, color_seg ;nope. Use color segment
- mov es, ax
- clc ;set carry to indicate color
- jmps set_video_exit ;and exit
-
- set_video_mono mov ax, mono_seg ;yep, use monochrome segment
- mov es, ax
- stc ;set carry to indicate monochrome
-
- set_video_exit pop ds
- ret
- endp
-
- ;========================================================
- ; CALC_OFFSET
- ;
- ; Input: AX screen column
- ; BX screen row
- ;
- ; Output: DI offset into video buffer
- ; AX trash
- ; BX trash
- ;
- ; Shifts and adds are used in place of multiplication
- ; for optimum speed. MUL requires a minimum of 74 clocks.
- ; The optimized "multiply by 160" sequence uses only 19 clocks.
- ;===============================================================
- calc_offset proc near
- dec bx ;rows past #1
- mov di, bx ;multiply row by 160
- shl di ;times 2
- shl di ;times 2 makes 4
- add di, bx ;1 more makes 5
- shl di ;times 2 makes 10
- shl di ;times 2 makes 20
- shl di ;times 2 makes 40
- shl di ;times 2 makes 80
- shl di ;times 2 makes 160
- dec ax ;columns past #1
- shl ax ;column x 2 (2 bytes/char)
- add di, ax ;di now has offset in buffer
- ret ;return to caller
- endp